home *** CD-ROM | disk | FTP | other *** search
- (* :Title: Signal Objects "Signal.m" *)
-
- (* :Authors: Brian Evans, James McClellan *)
-
- (* :Summary: To provide signal specification a la Cory Myers. *)
-
- (* :Context: SignalProcessing`ObjectOriented`Signal` *)
-
- (* :PackageVersion: 2.7 *)
-
- (*
- :Copyright: Copyright 1989-1991 by Brian L. Evans
- Georgia Tech Research Corporation
-
- Permission to use, copy, modify, and distribute this software
- and its documentation for any purpose and without fee is
- hereby granted, provided that the above copyright notice
- appear in all copies and that both that copyright notice and
- this permission notice appear in supporting documentation,
- and that the name of the Georgia Tech Research Corporation,
- Georgia Tech, or Georgia Institute of Technology not be used
- in advertising or publicity pertaining to distribution of the
- software without specific, written prior permission. Georgia
- Tech makes no representations about the suitability of this
- software for any purpose. It is provided "as is" without
- express or implied warranty.
- *)
-
- (* :History: *)
-
- (* :Keywords: *)
-
- (*
- :Source: Myers, C. {Signal Representation for Symbolic and
- Numeric Processing}. MIT Ph.D. Thesis. 1986.
- *)
-
- (* :Warning: *)
-
- (* :Mathematica Version: 1.2 or 2.0 *)
-
- (* :Limitation: *)
-
- (*
- :Discussion: All new functions have usage information.
- This file builds upon "Slot.m", "Support.m".
- This file is on the same level as "DSP.m", and "ZSupport.m"
- Signals have a variable number of slots.
- Slots defined by Cory Myers: (RealOrComplex --> DataType)
- Bandwidth
- CenterOfSymmetry
- End
- EndBandwidth
- Period
- Start
- StartBandwidth
- Support
- Symmetry
- Additional slots for all signals:
- CurrentValue
- Dimensions
- Length
- Additional slots for computable signals:
- FrequencyVariables
- Implementation
- OutOfDomainValue
- TheFunction
- TimeVariables
- ZTransData
- ZVariables
- Additional slots for stream signals:
- CurrentIndex
- Additional slots for array signals:
- Array
- Methods for signals:
- Fetch
- GetValue
- Z
- Methods for Stream signals:
- NextFun
- PreUpdateFunction
- PostUpdateFunction
- *)
-
- (*
- :Functions: ArraySignal
- ArraySignalQ
- ComputableSignalQ
- DiscreteTimeSignalQ
- Fetch
- GetValue
- IIRFilter
- MakeContinuousSignal
- MakeDigitalSignal
- MakeSignal
- MyMakeSignal
- PointwiseSignalQ
- SignalQ
- StreamSignal
- StreamSignalQ
- *)
-
-
-
- (* B E G I N P A C K A G E *)
-
- BeginPackage[ "SignalProcessing`ObjectOriented`Signal`",
- "SignalProcessing`ObjectOriented`Slot`",
- "SignalProcessing`ObjectOriented`StackQueue`",
- "SignalProcessing`Support`ROC`",
- "SignalProcessing`Support`DataType`",
- "SignalProcessing`Support`FilterSupport`",
- "SignalProcessing`Support`SigProc`",
- "SignalProcessing`Support`SupCode`" ]
-
-
- If [ TrueQ[ $VersionNumber >= 2.0 ],
- Off[ General::spell ];
- Off[ General::spell1 ] ];
-
-
- (* U S A G E I N F O R M A T I O N *)
-
- ArraySignal::usage =
- "ArraySignal[oldsig, start, end] returns a new signal which has \
- slots Start and End equal to start and end, respectively, and is \
- array-based (Implementation slot is Array)."
-
- ArraySignalQ::usage =
- "ArraySignalQ[signal] returns True if the signal is array-based, \
- which means that all signal values are computed at one time and \
- stored."
-
- CenterOfSymmetry::usage =
- "CenterOfSymmetry[signal] returns the center-of-symmetry of the \
- signal."
-
- ComputableSignalQ::usage =
- "ComputableSignalQ[signal] returns True if computational methods \
- like Fetch are supported for the signal. \
- This is true if the signal has an Implementation slot."
-
- DiscreteTimeSignalQ::usage =
- "DiscreteTimeSignalQ[signal] returns True if the signal is \
- a discrete-time signal."
-
- EndBandwith::usage =
- "EndBandwith[signal] retuns the end location of a signal's bandwidth. \
- In the case of signals that are not band-limited, \
- this function will return Infinity (the default)."
-
- Fetch::usage =
- "Fetch[signal, index] returns the value of the signal at index, \
- where index can be a number (for one-dimensional signals) or a \
- list of numbers (for multidimensional signals). Fetch only \
- works for computable signals which are arrayed, pointwise, and \
- stream signals. Stream signals also have an associated method \
- called FetchNext. If the signal is arrayed and if any one of \
- the indices is an infinity, then the value of the signal's \
- OutOfDomainValue slot will be returned."
-
- FetchArray::usage =
- "FetchArray[array_signal] ..."
-
- FetchNext::usage =
- "FetchNext[stream_signal] will return the next value in the stream \
- of data represented by stream_signal."
-
- IIRCoefficients::usage =
- "IIRCoefficients is a special slot for infinite-impulse response \
- digital filters. \
- It simply contains a list of feedback coefficients."
-
- IndependentVariable::usage =
- "IndependentVariable[signal] returns the independent variable(s) \
- involved in the signal's (functional) definition."
-
- IIRFilter::usage =
- "IIRFilter[p,a0,a][x] calculates the output of the IIR filter \
- at discrete time n, where the input at time n is x. The feedback\
- coefficients are in the a vector and each is scaled by a0. The \
- list p is a table of the last L outputs, where L is the number of \
- feedback coefficients."
-
- IIRPostUpdate::usage =
- "IIRPostUpdate is a special method just for IIR signals."
-
- MakeContinuousSignal::usage =
- "MakeContinuousSignal[] returns a signal object with the slot \
- CONTINUOUS set to True."
-
- MakeDigitalSignal::usage =
- "MakeDigitalSignal[] returns a signal object with the slot \
- DISCRETE set to True."
-
- MakeSignal::usage =
- "MakeSignal[] returns a signal object with one slot for system use. \
- MakeSignal[var] returns a signal object with slot \
- IndependentVariable set to var and with one slot defined for \
- system use. \
- MakeSignal[signal, n, property1, value, property2, value, ...] \
- can be used to define a signal as a function of n (the properties \
- are optional).
- If the signal is multidimensional, n will be a list of variables \
- (one for each dimension, like {n1, n2, n3} in the three-dimensional \
- case). \
- Possible signals include Impulse[n], Step[n], FIR[n, {h0, h1, ...}],
- and IIR[n, {a0, a1, ...}]. See MyMakeSignal."
-
- MyMakeSignal::usage =
- "MyMakeSignal[signal, var] extends the possibilities of MakeSignal. \
- It allows the definition of standard signals as a function of var. \
- Signals defined this way include FIR[n, h0, h1, ...] and \
- IIR[n, a0, a1, ...]."
-
- NextFun::usage =
- "NextFun is a method for stream-based signals describing how to \
- compute the next value."
-
- OutOfDomainValue::usage =
- "OutOfDomainValue[signal] is the value to return if the signal is \
- accessed outside of its region of support. \
- This value defaults to zero."
-
- PastValues::usage =
- "PastValues is a slot that remembers previously computed signal values."
-
- PointwiseSignal::usage =
- "PointwiseSignal is a type of signal in which signal values are \
- computed point-by-point. \
- Such a signal does not depend on previous outputs or inputs."
-
- PointwiseSignalQ::usage =
- "PointwiseSignalQ[signal] returns True if the values of the \
- signal are computed point-by-point, and the value at each \
- point is independent of other values of the signal."
-
- PostUpdateFunction::usage =
- "PostUpdateFunction is a method which is applied to signal after \
- each computation of a new signal value."
-
- PreUpdateFunction::usage =
- "PreUpdateFunction is a method which is applied to signal before \
- each computation of a new signal value."
-
- PrintName::usage =
- "PrintName[signal] is the name of the signal which is what is output \
- on the screen when the signal is to displayed."
-
- RealOrComplex::usage =
- "RealOrComplex[signal] returns True if the signal's output values \
- are real-valued or complex-valued."
-
- Self::usage =
- "Self is a pre-defined slot that is bound to the entire object \
- of which it is a member. \
- It can be used as a variable in methods and slots."
-
- Signal::usage =
- "A signal is an object with head Signal. \
- From the work of Cory Myers, possible slots include: \
- Bandwidth, CenterOfSymmetry, End, EndBandwidth, Period, Start, \
- StartBandwidth, Support, and Symmetry. \
- Possible additional slots are: \
- CurrentValue, DataType, Dimensions, FrequencyVariables, \
- Implementation, Length, OutOfDomainValue, TheFunction, \
- TimeVariables, ZTransData, ZVariables, CurrentIndex, \
- NextFun, PreUpdateFunction, and PostUpdateFunction. \
- Multidimensional signals are supported. See MakeSignal."
-
- SignalQ::usage =
- "SignalQ[x] returns True if the head of x is Signal."
-
- StartBandwith::usage =
- "StartBandwith[signal] returns the starting location of the bandwidth \
- of the signal. \
- For signals that are not bandlimited, \
- this method will return -Infinity which is the default value."
-
- StreamSignal::usage =
- "StreamSignal is a type of signal that computes its outputs one
- after another usually without reference to past values."
-
- StreamSignalQ::usage =
- "StreamSignalQ[signal] returns True if the values of signal are \
- computed one at a time in some order. \
- The value at each point can be dependent on previously-computed \
- values, state information, etc. \
- Signals generated by finite state machines are stream signals."
-
- (* E N D U S A G E I N F O R M A T I O N *)
-
-
- Begin["`Private`"]
-
- (* G L O B A L S *)
-
- arraysignal::dimensions = "Dimensions of start and end are different."
- Fetch::notcomputable = "Signal `` does not have computable values."
- MyMakeSignal::rect = "A rectangular window must have a positive length."
- oddlen::proplist = "Property list has odd number of terms."
- ztransform::notcomputable = "Signal `` does not have computable values."
- ztransform::notdiscrete = "`` is not a discrete-time signal."
- invztransform::notcomputable = "Signal `` does not have computable values."
- FIR::dimensions =
- "Using a one-dimensional variable for a multidimensional signal."
-
- (* Do not evaluate arguments to Signal[] because *)
- (* Signal is a data tag and not a function. *)
- DefObjectType[Signal]
-
- (* Prevents infinite loops; directs how operator[signal_object] is evaluated *)
- ClearStack[SignalOperatorSemaphore]
-
-
- (* S U P P O R T I N G R O U T I N E S *)
-
- (* ArraySignal -- end is non-inclusive *)
- ArraySignal[oldsig_, start_, end_, dims_] :=
- Block [ {signal},
- If [ ! SameQ[Dimensions[start], Dimensions[end]],
- Message[arraysignal::dimensions]; Return[Null] ];
- signal = oldsig;
- signal = AddSlot[signal, False, Start, start];
- AddSlot[signal, False, End, end];
- AddSlot[signal, False, Length, end - start];
- AddSlot[signal, False, Dimensions, dims];
- AddSlot[signal, False, CenterOfSymmetry, (end - start - 1)/2];
- AddSlot[signal, True, CurrentValue, 0];
- AddSlot[signal, False, Implementation, Array] ]
-
- (* ArraySignalQ *)
- ArraySignalQ[signal_] := SignalQ[signal] && SameQ[Implementation[signal], Array]
-
- (* ComputableSignalQ *)
- ComputableSignalQ[signal_] := HasSlotQ[signal, Implementation]
-
- (* DiscreteTimeSignalQ *)
- DiscreteTimeSignalQ[x_] := SignalQ[x] && DISCRETE[x] && SameQ[Domain[x], Time]
-
- (* GetValue -- two argument, three argument, and main versions *)
- Signal/: GetValue[Signal[slots__], index_] :=
- GetValue[Signal[slots], TimeVariables[signal], index]
-
- Signal/: GetValue[Signal[slots__], n_, index__] :=
- TheFunction[Signal[slots]] /.
- { ReplaceWith[n, index], Self -> Signal[slots] }
-
- (* IIRFilter :: input x[n], past n values p, feedback coefficients a *)
- IIRFilter[p_, a0_, a_][x_] := x - Dot[p, a] / a0;
-
- (* IIRPostUpdate *)
- SetAttributes[IIRPostUpdate, {HoldAll}]
-
- IIRPostUpdate[signal_] :=
- Block [ {newpast, pastvalues},
- pastvalues = PastValues[signal];
- If [ ListQ[pastvalues],
- newpast = RotateRight[pastvalues];
- newpast[[1]] = CurrentValue[signal],
- newpast = CurrentValue[signal] ];
- WriteSlot[signal, PastValues, newpast] ]
-
- (* MakeSignal *)
- MakeSignal[] := MakeObject[Signal]
- MakeSignal[FIR[n_, h_List]] := MakeSignal[FIR[n, h], n]
- MakeSignal[c_] :=
- Block [ {signal},
- signal = MakeSignal[];
- AddSlot[signal, False, TheFunction, c];
- AddSlot[signal, False, DataType, DataType[c]];
- AddSlot[signal, False, TimeVariables, n] ] /;
- ConstantQ[c]
- MakeSignal[var_] :=
- Block [ {signal},
- signal = MakeSignal[];
- AddSlot[signal, False, TimeVariables, var] ]
- MakeSignal[x_, n_:Global`n] :=
- Block [ {datatype, signal},
- signal = MyMakeSignal[x, n];
- If [ SameQ[Head[signal], MyMakeSignal],
- signal = MakeSignal[n];
- AddSlot[signal, False, TheFunction, x] ];
- If [ ! HasSlotQ[signal, DataType] && HasSlotQ[signal, TheFunction],
- datatype = DataType[ReadSlot[signal, TheFunction]];
- If [ DataTypeQ[datatype],
- AddSlot[signal, False, DataType, datatype] ] ];
- signal ]
- MakeSignal[x_, n_, properties__] :=
- Block [ {prop, signal},
- signal = MakeSignal[x, n];
- proplist = ToList[properties];
- len = Length[proplist];
- If [ OddQ[len], Message[oddlen::proplist] ];
- For [ prop = 1, prop < len, prop += 2,
- WriteSlot[signal, proplist[[prop]], proplist[[prop+1]]] ];
- signal ]
-
- (* MakeDigitalSignal and MakeContinuousSignal *)
- MakeDigitalSignal[n_:Global`n] :=
- Block [ {signal},
- signal = MakeSignal[];
- signal = AddSlot[signal, False, TimeVariables, n];
- AddSlot[signal, False, DISCRETE, True] ]
- MakeContinuousSignal[t_:Global`t] :=
- Block [ {signal},
- signal = MakeSignal[];
- signal = AddSlot[signal, False, TimeVariables, t];
- AddSlot[signal, False, CONTINUOUS, True] ]
-
- (* PointwiseSignalQ *)
- PointwiseSignalQ[signal_] := SignalQ[signal] && SameQ[Implementation[signal], Pointwise]
-
- (* SignalQ *)
- SignalQ[x_] := SameQ[Head[x], Signal]
-
- (* StreamSignal *)
- StreamSignal[signal_, start_, end_] :=
- Block [ {newsig},
- newsig = signal;
- AddSlot[newsig, False, Start, start];
- AddSlot[newsig, False, End, end];
- AddSlot[newsig, True, CurrentIndex, start - 1];
- AddSlot[newsig, False, Implementation, Stream] ]
-
- (* StreamSignalQ *)
- StreamSignalQ[signal_] := SameQ[Implementation[signal], Stream]
-
-
- (* B A S I C S I G N A L S *)
-
- (* FIR[n, {h0, h1, ...}] is the impulse response of a finite *)
- (* impulse response filter with coefficients h0, h1, ... *)
- MyMakeSignal[FIR[n_, h_], n_] :=
- Block [ {dims, dimensions, hlist, signal, start},
- hlist = ToList[h];
- dimensions = Dimensions[hlist];
- dims = Length[dimensions];
- start = Table[0, {dims}];
- If [ dims == 1,
- start = 0; dimensions = Length[hlist] ];
- If [ dims > 1 && AtomQ[n],
- Message[FIR::dimensions] ];
- signal = ArraySignal[MakeDigitalSignal[n], start,
- dimensions, dims];
- AddSlot[signal, False, PrintName, FIR[n, h]];
- AddSlot[signal, False, TheFunction,
- SequenceToFunction[hlist, n]] ];
-
- (* IIR[n, a0, a1, a2, ...] is the impulse response of an *)
- (* IIR filter with feedback coefficients -a1, -a2, ... *)
- (* The coding trick here is the use of Self. That is, *)
- (* PastValues[Self, ...] will remain unevaluated until *)
- (* GetValue is called by the user. *)
- MyMakeSignal[IIR[n_, a__]] := MyMakeSignal[IIR[n, a], n]
- MyMakeSignal[IIR[n_, a__], n_] :=
- Block [ {alist, index, len, signal, z = Global`z, zdenom, zerocount},
- alist = ToList[a];
- len = Length[alist];
- signal = MakeDigitalSignal[n];
- signal = StreamSignal[signal, 0, Infinity];
- AddSlot[signal, False, IIRCoefficients, alist];
- AddSlot[signal, True, CurrentValue, 0];
- If [ len <= 2,
- AddSlot[signal, True, PastValues, 0],
- AddSlot[signal, True, PastValues,
- Table[0, {zerocount, 2, len}]] ];
- AddSlot[signal, False, TheFunction,
- IIRFilter[PastValues[Self],
- First[alist],
- Rest[alist]][Impulse[n]]];
- AddSlot[signal, False, PostUpdateFunction, IIRPostUpdate];
- zdenom = alist[[1]] +
- Apply[ Plus,
- Table[ -alist[[index]] z^(1-index),
- {index, 2, len} ] ];
- zobject = ZTransData[ 1 / zdenom, Rminus[0],
- Rplus[Infinity], ZVariables[z] ];
- AddSlot[signal, False, PrintName, IIR[n, a]];
- AddSlot[signal, False, Head[zobject], GetArgs[zobject]] ]
-
-
- (* S I G N A L M E T H O D S *)
-
-
- (* Fetching signal values *)
-
- (* Fetch fetches a signal's value at the passed index: *)
- (* [1] the signal's PreUpdateFunction is called if it exists, *)
- (* [2] the signal's value at the passed index is calculated, *)
- (* [3] the signal's PostUpdateFunction is called if it exists. *)
- (* The new signal is returned, the signal value being placed in *)
- (* slot CurrentValue. *)
-
- SetAttributes[Fetch, {HoldFirst}]
- SetAttributes[FetchArray, {HoldFirst}]
- SetAttributes[FetchNext, {HoldFirst}]
-
- (* Convert all multidimensional indices into a list form *)
- Fetch[signal_, i1_, indices__] :=
- Fetch[signal, {i1, indices}] /;
- SignalQ[signal]
-
- (* Illegal to Fetch on an abstract signal or other non-computable signal *)
- Fetch[signal_, index_] :=
- Message[Fetch::notcomputable, Signal[slots]] /;
- SignalQ[signal] && ! ComputableSignalQ[signal]
-
- (* Fetch on Pointwise signal *)
- Fetch[signal_, index_] :=
- Block [ {value},
- value = GetValue[signal, index];
- signal = WriteSlot[signal, CurrentValue, value];
- value ] /;
- PointwiseSignalQ[signal]
-
- (* Fetch on Stream signal: signal is not evaluated *)
- FetchNext[signal_] :=
- Block [ {index, newval},
- If [ HasSlotQ[signal, PreUpdateFunction],
- PreUpdateFunction[signal][signal],
- AppendSlot[signal, CurrentIndex, Plus, 1] ];
- index = CurrentIndex[signal];
- signal = WriteSlot[signal, CurrentIndex, index];
- newval = GetValue[signal, index];
- WriteSlot[signal, CurrentValue, newval];
- If [ HasSlotQ[signal, PostUpdateFunction],
- PostUpdateFunction[signal][signal] ];
- newval ] /;
- StreamSignalQ[signal]
-
- Fetch[signal_, endindex_] :=
- Block [ {curindex, index},
- curindex = CurrentIndex[signal];
- nextfun = NextFun[signal];
- If [ TrueQ[index < curindex],
- signal = TableLookup[signal, curindex],
- For [ index = curindex,
- ! SameQ[index, endindex],
- index = nextfun[index],
- FetchNext[signal] ] ];
- CurrentValue[signal] ] /;
- StreamSignalQ[signal]
-
- (* Fetch on Array signal *)
- FetchArray[signal_] :=
- Block [ {table},
- thevalue[subs__] := GetValue[signal, subs];
- table = Array[thevalue, Length[signal], Start[signal]];
- signal = AddSlot[signal, False, Array, table] ] /;
- ArraySignalQ[signal]
-
- Fetch[signal_, index_] :=
- Block [ {value},
- If [ ! HasSlotQ[signal, Array],
- FetchArray[signal] ];
- value = TableLookup[1 + index - Start[signal],
- Array[signal],
- Length[signal],
- OutOfDomainValue[signal] ];
- signal = WriteSlot[signal, CurrentValue, value];
- value ] /;
- ArraySignalQ[signal]
-
-
- (* Extensions of built-in functions *)
-
- (* Format *)
- Signal/: Format[ Signal[slots__] ] :=
- PrintName[Signal[slots]] /;
- HasSlotQ[Signal[slots], PrintName]
-
-
- (* Extensions to "DataType.m" *)
-
- Signal/: DataType[ Signal[slots__] ] :=
- Signal[slots__] :> ReadSlot[Signal[slots], DataType] /;
- HasSlotQ[Signal[slots], DataType]
- Signal/: DataType[ Signal[slots__] ] :=
- ReadSlot[Signal[slots], TheFunction] /;
- HasSlotQ[Signal[slots], TheFunction]
-
- (* ConstantQ *)
- Signal/: ConstantQ[ Signal[slots__] ] :=
- MyFreeQ[TheFunction[Signal[slots]], TimeVariables[Signal[slots]]]
-
- (* IsComplexQ *)
- Signal/: IsComplexQ[ Signal[slots__] ] :=
- SameQ[DataType[Signal[slots]], Complex]
-
- (* IsImaginaryQ *)
- Signal/: IsImaginaryQ[ Signal[slots__] ] :=
- SameQ[DataType[Signal[slots]], Imaginary]
-
- (* IsRealQ *)
- Signal/: IsRealQ[ Signal[slots__] ] :=
- SameQ[DataType[Signal[slots]], Real]
-
-
- (* Extensions of "SigProc.m" *)
-
- (* Difference *)
- Difference/: Expand[Difference[k_,n_][Signal[slots__]]] :=
- Expand[Difference[k,n][TheFunction[Signal[slots]]]]
-
- (* Shift *)
- Shift/: Expand[Shift[k_,n_][Signal[slots__]]] :=
- Block [ {newsig},
- newsig = Signal[slots];
- vars = TimeVariables[newsig];
- WriteSlot[newsig,
- TheFunction,
- TheFunction[newsig] /. vars -> vars + k] ]
-
- (* Summation *)
- Signal/: Summation[i_][Signal[slots__]] :=
- Summation[i, TimeVariables[Signal[slots]]] [Signal[slots]]
-
- (* Apply any operator to a Signal object -- without the semaphore, *)
- (* an infinite loop will result. If the signal has a slot with the *)
- (* same name as the operator, the value of the slot is returned. *)
- (* Otherwise, it is assumed that operator is a method and the *)
- (* function operator will be applied to the signal. *)
- Signal/: operator_[ Signal[slots__] ] :=
- Block [ {result, signal},
- Push[SignalOperatorSemaphore, operator];
- signal = Signal[slots];
- If [ HasSlotQ[signal, operator],
- result = ReadSlot[signal, operator],
- result = operator[signal] ];
- Pop[SignalOperatorSemaphore];
- result ] /;
- ! MemberQ[SignalOperatorSemaphore, operator]
-
-
- (* Interface to the forward z-transform package *)
- (*
- PrependTo[ZTransformInterfaceRules,
- ztrans[x_, args__] :>
- Which [ ! HasSlotQ[x, TheFunction],
- MyMessage[ztransform::notcomputable, Null, x],
- TrueQ[ DISCRETE[x] ],
- ZTransform[ReadSlot[x, TheFunction]],
- True,
- MyMessage[ztransform::notdiscrete, Null, x] ] /;
- SignalQ[x] ]
-
- PrependTo[InvZTransformInterfaceRules,
- zinverse[x_, args__] :>
- InvZTransform[ReadSlot[x, ZTransData], args] /;
- SignalQ[x] && HasSlotQ[x, ZTransData] ]
- *)
-
-
- (* D E F A U L T S L O T V A L U E S *)
-
- DefaultSlot[Signal, Bandwidth, Infinity]
- DefaultSlot[Signal, CenterOfSymmetry, None]
- DefaultSlot[Signal, DataType, Complex]
- DefaultSlot[Signal, End, Infinity]
- DefaultSlot[Signal, EndBandwidth, Infinity]
- DefaultSlot[Signal, Period, Infinity]
- DefaultSlot[Signal, Start, -Infinity]
- DefaultSlot[Signal, StartBandwidth, -Infinity]
- DefaultSlot[Signal, Support, { -Infinity, Infinity } ]
- DefaultSlot[Signal, Symmetry, None]
-
- DefaultSlot[Signal, CurrentValue, Null]
- DefaultSlot[Signal, Dimensions, 1]
- DefaultSlot[Signal, Length, 0]
- DefaultSlot[Signal, OutOfDomainValue, 0]
-
-
- (* Determination of Variables *)
- defaultsignalvars[x_, dv_, cv_] :=
- Block [ {numdims},
- numdims = ReadSlot[x, Dimensions];
- Which [ TrueQ[ DISCRETE[x] ],
- DummyVariables[numdims, dv],
- TrueQ[ CONTINUOUS[x] ],
- DummyVariables[numdims, cv],
- True,
- DummyVariables[numdims, dv] ] ]
-
- TimeVariables[x_] :=
- ReadSlot[x, TimeVariables] /;
- HasSlotQ[x, TimeVariables]
- TimeVariables[x_] :=
- defaultsignalvars[x, Global`n, Global`t] /;
- HasSlotQ[x, Dimensions]
-
- ZVariables[x_] :=
- ReadSlot[x, ZVariables] /;
- HasSlotQ[x, ZVariables]
- ZVariables[x_] :=
- DummyVariables[Length[ReadSlot[x, TimeVariables]], z] /;
- HasSlotQ[x, Dimensions] && DISCRETE[x] && HasSlotQ[x, TimeVariables]
-
- FrequencyVariables[x_] :=
- ReadSlot[x, FrequencyVariables] /;
- HasSlotQ[x, FrequencyVariables]
- FrequencyVariables[x_] :=
- defaultsignalvars[x, Global`k, Global`w] /;
- HasSlotQ[x, Dimensions]
-
-
- (* E N D P A C K A G E *)
-
- End[]
- EndPackage[]
-
- If [ TrueQ[ $VersionNumber >= 2.0 ],
- On[ General::spell ];
- On[ General::spell1 ] ];
-
-
- (* W R I T E P R O T E C T I O N *)
-
- Combine[ SPsignals, { ArraySignal, PointwiseSignal, StreamSignal } ]
-
- Combine[SPfunctions,
- List[ ArraySignalQ, ComputableSignalQ, IIRFilter,
- MakeContinuousSignal, MakeDigitalSignal, MakeSignal,
- PointwiseSignalQ, SignalQ, StreamSignalQ ] ]
-
-
- (* E N D I N G M E S S A G E *)
-
- Print[ "Signal objects are loaded." ]
- Null
-